home *** CD-ROM | disk | FTP | other *** search
/ HPAVC / HPAVC CD-ROM.iso / BF_SDK11.ZIP / BFENG386.ASM < prev    next >
Assembly Source File  |  1996-06-05  |  30KB  |  910 lines

  1.  
  2. ; BFENG386.ASM
  3. ; Implementation of the Blowfish-Engine        V 2.2
  4.  
  5. ; (c)1996  Markus Hahn & Cedric Reinartz
  6.  
  7. ; !!!       All restrictions in BF-SDK.TXT apply        !!!
  8.  
  9. ; Flags
  10. ; -----
  11. ; You can control the behaviour of this modul from outside.
  12. ; If you don`t do this, the default values are set here:
  13.  
  14.     ifndef noLOOP
  15.     noLOOP        equ    1    ; 1 = enrolled LOOPs
  16.                     ; 0 = gives shorter code but has a
  17.                     ;     20% speed penalty
  18.     endif
  19.     ifndef rnds
  20.         rnds            equ     3       ; 1 = 16 rounds (always)
  21.                                         ; 2 = 32 rounds (always)
  22.                     ; 3 = 16 is default, but you can change
  23.                                         ;     to 32 at runtime by software
  24.     endif
  25.  
  26.     ;useSmall    equ    1    ; Large Model is used
  27.                     ; If defined Small model is used
  28.     
  29.     ;noPub        equ    1    ; Functions are exported
  30.                     ; If defined you can INCLUDE this
  31.                     ; code to your main-programm and you
  32.                     ; do not need to export the functions.
  33.                     ; So you can hide them and give your
  34.                     ; *.OBJ away.
  35.  
  36. if rnds eq 1
  37.     PSBox_size    equ 18+4*256    ; Boxsize for 16 Rounds
  38. else
  39.     PSBox_size    equ 34+4*256    ; Boxsize for a max of 32 Rounds
  40. endif
  41.  
  42.  
  43. ifndef useSmall
  44.         .MODEL LARGE
  45.     sofs equ 0
  46. else
  47.     .model small
  48.     sofs equ -2
  49. endif
  50.         .386
  51.  
  52. ifndef noPub
  53.     ; exported Functions ...
  54.         PUBLIC Blowfish_GetBoxPointer
  55.         PUBLIC Blowfish_GetBoxes
  56.         PUBLIC Blowfish_SetBoxes
  57.         PUBLIC Blowfish_Init
  58.         PUBLIC Blowfish_ECBEncrypt
  59.         PUBLIC Blowfish_ECBDecrypt
  60.         PUBLIC Blowfish_CBCEncrypt
  61.         PUBLIC Blowfish_CBCDecrypt
  62.         PUBLIC Blowfish_Done
  63.         PUBLIC Blowfish_SetRounds
  64.         PUBLIC Blowfish_WeakKey
  65.  
  66.     _end macro        ; I think it is the only method to terminate
  67.      END            ; this code with an END instruction
  68.     endm
  69. else
  70.     _end macro        ; or not.
  71.     endm
  72. endif
  73.  
  74.         .DATA
  75.  
  76. ; P- and S-Boxes are predefined.
  77. ; Boxsizes :       - P-Boxen : 18 or 34 Longints/DWords
  78. ;                  - S-Boxen :    4*256 Longints/DWords
  79. ;                  Size and contents of SBoxes is always the same.
  80. ;                  For 32 Round (rnds= 2 or 3) size and contents of
  81. ;                  PBox extends
  82. ; Attention! Do not place anything between the boxes
  83.  
  84.     align    32
  85.  
  86. pbox    dd 0243f6a88h, 085a308d3h, 013198a2eh, 003707344h, 0a4093822h, 0299f31d0h
  87.     dd 0082efa98h, 0ec4e6c89h, 0452821e6h, 038d01377h, 0be5466cfh, 034e90c6ch
  88.     dd 0c0ac29b7h, 0c97c50ddh, 03f84d5b5h, 0b5470917h, 09216d5d9h, 08979fb1bh
  89. ife rnds eq 1
  90.     dd 0B83ACB02h, 02002397Ah, 06EC6FB5Bh, 0FFCFD4DDh, 04CBF5ED1h, 0F43FE582h
  91.     dd 03EF4E823h, 02D152AF0h, 0E718C970h, 059BD9820h, 01F4A9D62h, 0E7A529BAh
  92.     dd 089E1248Dh, 03BF88656h, 0C5114D0Eh, 0BC4CEE16h
  93. endif
  94. sbox1    dd 0d1310ba6h, 098dfb5ach, 02ffd72dbh, 0d01adfb7h, 0b8e1afedh, 06a267e96h
  95.     dd 0ba7c9045h, 0f12c7f99h, 024a19947h, 0b3916cf7h, 00801f2e2h, 0858efc16h
  96.     dd 0636920d8h, 071574e69h, 0a458fea3h, 0f4933d7eh, 00d95748fh, 0728eb658h
  97.     dd 0718bcd58h, 082154aeeh, 07b54a41dh, 0c25a59b5h, 09c30d539h, 02af26013h
  98.     dd 0c5d1b023h, 0286085f0h, 0ca417918h, 0b8db38efh, 08e79dcb0h, 0603a180eh
  99.     dd 06c9e0e8bh, 0b01e8a3eh, 0d71577c1h, 0bd314b27h, 078af2fdah, 055605c60h
  100.     dd 0e65525f3h, 0aa55ab94h, 057489862h, 063e81440h, 055ca396ah, 02aab10b6h
  101.     dd 0b4cc5c34h, 01141e8ceh, 0a15486afh, 07c72e993h, 0b3ee1411h, 0636fbc2ah
  102.     dd 02ba9c55dh, 0741831f6h, 0ce5c3e16h, 09b87931eh, 0afd6ba33h, 06c24cf5ch
  103.     dd 07a325381h, 028958677h, 03b8f4898h, 06b4bb9afh, 0c4bfe81bh, 066282193h
  104.     dd 061d809cch, 0fb21a991h, 0487cac60h, 05dec8032h, 0ef845d5dh, 0e98575b1h
  105.     dd 0dc262302h, 0eb651b88h, 023893e81h, 0d396acc5h, 00f6d6ff3h, 083f44239h
  106.     dd 02e0b4482h, 0a4842004h, 069c8f04ah, 09e1f9b5eh, 021c66842h, 0f6e96c9ah
  107.     dd 0670c9c61h, 0abd388f0h, 06a51a0d2h, 0d8542f68h, 0960fa728h, 0ab5133a3h
  108.     dd 06eef0b6ch, 0137a3be4h, 0ba3bf050h, 07efb2a98h, 0a1f1651dh, 039af0176h
  109.     dd 066ca593eh, 082430e88h, 08cee8619h, 0456f9fb4h, 07d84a5c3h, 03b8b5ebeh
  110.     dd 0e06f75d8h, 085c12073h, 0401a449fh, 056c16aa6h, 04ed3aa62h, 0363f7706h
  111.     dd 01bfedf72h, 0429b023dh, 037d0d724h, 0d00a1248h, 0db0fead3h, 049f1c09bh
  112.     dd 0075372c9h, 080991b7bh, 025d479d8h, 0f6e8def7h, 0e3fe501ah, 0b6794c3bh
  113.     dd 0976ce0bdh, 004c006bah, 0c1a94fb6h, 0409f60c4h, 05e5c9ec2h, 0196a2463h
  114.     dd 068fb6fafh, 03e6c53b5h, 01339b2ebh, 03b52ec6fh, 06dfc511fh, 09b30952ch
  115.     dd 0cc814544h, 0af5ebd09h, 0bee3d004h, 0de334afdh, 0660f2807h, 0192e4bb3h
  116.     dd 0c0cba857h, 045c8740fh, 0d20b5f39h, 0b9d3fbdbh, 05579c0bdh, 01a60320ah
  117.     dd 0d6a100c6h, 0402c7279h, 0679f25feh, 0fb1fa3cch, 08ea5e9f8h, 0db3222f8h
  118.     dd 03c7516dfh, 0fd616b15h, 02f501ec8h, 0ad0552abh, 0323db5fah, 0fd238760h
  119.     dd 053317b48h, 03e00df82h, 09e5c57bbh, 0ca6f8ca0h, 01a87562eh, 0df1769dbh
  120.     dd 0d542a8f6h, 0287effc3h, 0ac6732c6h, 08c4f5573h, 0695b27b0h, 0bbca58c8h
  121.     dd 0e1ffa35dh, 0b8f011a0h, 010fa3d98h, 0fd2183b8h, 04afcb56ch, 02dd1d35bh
  122.     dd 09a53e479h, 0b6f84565h, 0d28e49bch, 04bfb9790h, 0e1ddf2dah, 0a4cb7e33h
  123.     dd 062fb1341h, 0cee4c6e8h, 0ef20cadah, 036774c01h, 0d07e9efeh, 02bf11fb4h
  124.     dd 095dbda4dh, 0ae909198h, 0eaad8e71h, 06b93d5a0h, 0d08ed1d0h, 0afc725e0h
  125.     dd 08e3c5b2fh, 08e7594b7h, 08ff6e2fbh, 0f2122b64h, 08888b812h, 0900df01ch
  126.     dd 04fad5ea0h, 0688fc31ch, 0d1cff191h, 0b3a8c1adh, 02f2f2218h, 0be0e1777h
  127.     dd 0ea752dfeh, 08b021fa1h, 0e5a0cc0fh, 0b56f74e8h, 018acf3d6h, 0ce89e299h
  128.     dd 0b4a84fe0h, 0fd13e0b7h, 07cc43b81h, 0d2ada8d9h, 0165fa266h, 080957705h
  129.     dd 093cc7314h, 0211a1477h, 0e6ad2065h, 077b5fa86h, 0c75442f5h, 0fb9d35cfh
  130.     dd 0ebcdaf0ch, 07b3e89a0h, 0d6411bd3h, 0ae1e7e49h, 000250e2dh, 02071b35eh
  131.     dd 0226800bbh, 057b8e0afh, 02464369bh, 0f009b91eh, 05563911dh, 059dfa6aah
  132.     dd 078c14389h, 0d95a537fh, 0207d5ba2h, 002e5b9c5h, 083260376h, 06295cfa9h
  133.     dd 011c81968h, 04e734a41h, 0b3472dcah, 07b14a94ah, 01b510052h, 09a532915h
  134.     dd 0d60f573fh, 0bc9bc6e4h, 02b60a476h, 081e67400h, 008ba6fb5h, 0571be91fh
  135.     dd 0f296ec6bh, 02a0dd915h, 0b6636521h, 0e7b9f9b6h, 0ff34052eh, 0c5855664h
  136.     dd 053b02d5dh, 0a99f8fa1h, 008ba4799h, 06e85076ah
  137. sbox2    dd 04b7a70e9h, 0b5b32944h
  138.     dd 0db75092eh, 0c4192623h, 0ad6ea6b0h, 049a7df7dh, 09cee60b8h, 08fedb266h
  139.     dd 0ecaa8c71h, 0699a17ffh, 05664526ch, 0c2b19ee1h, 0193602a5h, 075094c29h
  140.     dd 0a0591340h, 0e4183a3eh, 03f54989ah, 05b429d65h, 06b8fe4d6h, 099f73fd6h
  141.     dd 0a1d29c07h, 0efe830f5h, 04d2d38e6h, 0f0255dc1h, 04cdd2086h, 08470eb26h
  142.     dd 06382e9c6h, 0021ecc5eh, 009686b3fh, 03ebaefc9h, 03c971814h, 06b6a70a1h
  143.     dd 0687f3584h, 052a0e286h, 0b79c5305h, 0aa500737h, 03e07841ch, 07fdeae5ch
  144.     dd 08e7d44ech, 05716f2b8h, 0b03ada37h, 0f0500c0dh, 0f01c1f04h, 00200b3ffh
  145.     dd 0ae0cf51ah, 03cb574b2h, 025837a58h, 0dc0921bdh, 0d19113f9h, 07ca92ff6h
  146.     dd 094324773h, 022f54701h, 03ae5e581h, 037c2dadch, 0c8b57634h, 09af3dda7h
  147.     dd 0a9446146h, 00fd0030eh, 0ecc8c73eh, 0a4751e41h, 0e238cd99h, 03bea0e2fh
  148.     dd 03280bba1h, 0183eb331h, 04e548b38h, 04f6db908h, 06f420d03h, 0f60a04bfh
  149.     dd 02cb81290h, 024977c79h, 05679b072h, 0bcaf89afh, 0de9a771fh, 0d9930810h
  150.     dd 0b38bae12h, 0dccf3f2eh, 05512721fh, 02e6b7124h, 0501adde6h, 09f84cd87h
  151.     dd 07a584718h, 07408da17h, 0bc9f9abch, 0e94b7d8ch, 0ec7aec3ah, 0db851dfah
  152.     dd 063094366h, 0c464c3d2h, 0ef1c1847h, 03215d908h, 0dd433b37h, 024c2ba16h
  153.     dd 012a14d43h, 02a65c451h, 050940002h, 0133ae4ddh, 071dff89eh, 010314e55h
  154.     dd 081ac77d6h, 05f11199bh, 0043556f1h, 0d7a3c76bh, 03c11183bh, 05924a509h
  155.     dd 0f28fe6edh, 097f1fbfah, 09ebabf2ch, 01e153c6eh, 086e34570h, 0eae96fb1h
  156.     dd 0860e5e0ah, 05a3e2ab3h, 0771fe71ch, 04e3d06fah, 02965dcb9h, 099e71d0fh
  157.     dd 0803e89d6h, 05266c825h, 02e4cc978h, 09c10b36ah, 0c6150ebah, 094e2ea78h
  158.     dd 0a5fc3c53h, 01e0a2df4h, 0f2f74ea7h, 0361d2b3dh, 01939260fh, 019c27960h
  159.     dd 05223a708h, 0f71312b6h, 0ebadfe6eh, 0eac31f66h, 0e3bc4595h, 0a67bc883h
  160.     dd 0b17f37d1h, 0018cff28h, 0c332ddefh, 0be6c5aa5h, 065582185h, 068ab9802h
  161.     dd 0eecea50fh, 0db2f953bh, 02aef7dadh, 05b6e2f84h, 01521b628h, 029076170h
  162.     dd 0ecdd4775h, 0619f1510h, 013cca830h, 0eb61bd96h, 00334fe1eh, 0aa0363cfh
  163.     dd 0b5735c90h, 04c70a239h, 0d59e9e0bh, 0cbaade14h, 0eecc86bch, 060622ca7h
  164.     dd 09cab5cabh, 0b2f3846eh, 0648b1eafh, 019bdf0cah, 0a02369b9h, 0655abb50h
  165.     dd 040685a32h, 03c2ab4b3h, 0319ee9d5h, 0c021b8f7h, 09b540b19h, 0875fa099h
  166.     dd 095f7997eh, 0623d7da8h, 0f837889ah, 097e32d77h, 011ed935fh, 016681281h
  167.     dd 00e358829h, 0c7e61fd6h, 096dedfa1h, 07858ba99h, 057f584a5h, 01b227263h
  168.     dd 09b83c3ffh, 01ac24696h, 0cdb30aebh, 0532e3054h, 08fd948e4h, 06dbc3128h
  169.     dd 058ebf2efh, 034c6ffeah, 0fe28ed61h, 0ee7c3c73h, 05d4a14d9h, 0e864b7e3h
  170.     dd 042105d14h, 0203e13e0h, 045eee2b6h, 0a3aaabeah, 0db6c4f15h, 0facb4fd0h
  171.     dd 0c742f442h, 0ef6abbb5h, 0654f3b1dh, 041cd2105h, 0d81e799eh, 086854dc7h
  172.     dd 0e44b476ah, 03d816250h, 0cf62a1f2h, 05b8d2646h, 0fc8883a0h, 0c1c7b6a3h
  173.     dd 07f1524c3h, 069cb7492h, 047848a0bh, 05692b285h, 0095bbf00h, 0ad19489dh
  174.     dd 01462b174h, 023820e00h, 058428d2ah, 00c55f5eah, 01dadf43eh, 0233f7061h
  175.     dd 03372f092h, 08d937e41h, 0d65fecf1h, 06c223bdbh, 07cde3759h, 0cbee7460h
  176.     dd 04085f2a7h, 0ce77326eh, 0a6078084h, 019f8509eh, 0e8efd855h, 061d99735h
  177.     dd 0a969a7aah, 0c50c06c2h, 05a04abfch, 0800bcadch, 09e447a2eh, 0c3453484h
  178.     dd 0fdd56705h, 00e1e9ec9h, 0db73dbd3h, 0105588cdh, 0675fda79h, 0e3674340h
  179.     dd 0c5c43465h, 0713e38d8h, 03d28f89eh, 0f16dff20h, 0153e21e7h, 08fb03d4ah
  180.     dd 0e6e39f2bh, 0db83adf7h
  181. sbox3    dd 0e93d5a68h, 0948140f7h, 0f64c261ch, 094692934h
  182.     dd 0411520f7h, 07602d4f7h, 0bcf46b2eh, 0d4a20068h, 0d4082471h, 03320f46ah
  183.     dd 043b7d4b7h, 0500061afh, 01e39f62eh, 097244546h, 014214f74h, 0bf8b8840h
  184.     dd 04d95fc1dh, 096b591afh, 070f4ddd3h, 066a02f45h, 0bfbc09ech, 003bd9785h
  185.     dd 07fac6dd0h, 031cb8504h, 096eb27b3h, 055fd3941h, 0da2547e6h, 0abca0a9ah
  186.     dd 028507825h, 0530429f4h, 00a2c86dah, 0e9b66dfbh, 068dc1462h, 0d7486900h
  187.     dd 0680ec0a4h, 027a18deeh, 04f3ffea2h, 0e887ad8ch, 0b58ce006h, 07af4d6b6h
  188.     dd 0aace1e7ch, 0d3375fech, 0ce78a399h, 0406b2a42h, 020fe9e35h, 0d9f385b9h
  189.     dd 0ee39d7abh, 03b124e8bh, 01dc9faf7h, 04b6d1856h, 026a36631h, 0eae397b2h
  190.     dd 03a6efa74h, 0dd5b4332h, 06841e7f7h, 0ca7820fbh, 0fb0af54eh, 0d8feb397h
  191.     dd 0454056ach, 0ba489527h, 055533a3ah, 020838d87h, 0fe6ba9b7h, 0d096954bh
  192.     dd 055a867bch, 0a1159a58h, 0cca92963h, 099e1db33h, 0a62a4a56h, 03f3125f9h
  193.     dd 05ef47e1ch, 09029317ch, 0fdf8e802h, 004272f70h, 080bb155ch, 005282ce3h
  194.     dd 095c11548h, 0e4c66d22h, 048c1133fh, 0c70f86dch, 007f9c9eeh, 041041f0fh
  195.     dd 0404779a4h, 05d886e17h, 0325f51ebh, 0d59bc0d1h, 0f2bcc18fh, 041113564h
  196.     dd 0257b7834h, 0602a9c60h, 0dff8e8a3h, 01f636c1bh, 00e12b4c2h, 002e1329eh
  197.     dd 0af664fd1h, 0cad18115h, 06b2395e0h, 0333e92e1h, 03b240b62h, 0eebeb922h
  198.     dd 085b2a20eh, 0e6ba0d99h, 0de720c8ch, 02da2f728h, 0d0127845h, 095b794fdh
  199.     dd 0647d0862h, 0e7ccf5f0h, 05449a36fh, 0877d48fah, 0c39dfd27h, 0f33e8d1eh
  200.     dd 00a476341h, 0992eff74h, 03a6f6eabh, 0f4f8fd37h, 0a812dc60h, 0a1ebddf8h
  201.     dd 0991be14ch, 0db6e6b0dh, 0c67b5510h, 06d672c37h, 02765d43bh, 0dcd0e804h
  202.     dd 0f1290dc7h, 0cc00ffa3h, 0b5390f92h, 0690fed0bh, 0667b9ffbh, 0cedb7d9ch
  203.     dd 0a091cf0bh, 0d9155ea3h, 0bb132f88h, 0515bad24h, 07b9479bfh, 0763bd6ebh
  204.     dd 037392eb3h, 0cc115979h, 08026e297h, 0f42e312dh, 06842ada7h, 0c66a2b3bh
  205.     dd 012754ccch, 0782ef11ch, 06a124237h, 0b79251e7h, 006a1bbe6h, 04bfb6350h
  206.     dd 01a6b1018h, 011caedfah, 03d25bdd8h, 0e2e1c3c9h, 044421659h, 00a121386h
  207.     dd 0d90cec6eh, 0d5abea2ah, 064af674eh, 0da86a85fh, 0bebfe988h, 064e4c3feh
  208.     dd 09dbc8057h, 0f0f7c086h, 060787bf8h, 06003604dh, 0d1fd8346h, 0f6381fb0h
  209.     dd 07745ae04h, 0d736fccch, 083426b33h, 0f01eab71h, 0b0804187h, 03c005e5fh
  210.     dd 077a057beh, 0bde8ae24h, 055464299h, 0bf582e61h, 04e58f48fh, 0f2ddfda2h
  211.     dd 0f474ef38h, 08789bdc2h, 05366f9c3h, 0c8b38e74h, 0b475f255h, 046fcd9b9h
  212.     dd 07aeb2661h, 08b1ddf84h, 0846a0e79h, 0915f95e2h, 0466e598eh, 020b45770h
  213.     dd 08cd55591h, 0c902de4ch, 0b90bace1h, 0bb8205d0h, 011a86248h, 07574a99eh
  214.     dd 0b77f19b6h, 0e0a9dc09h, 0662d09a1h, 0c4324633h, 0e85a1f02h, 009f0be8ch
  215.     dd 04a99a025h, 01d6efe10h, 01ab93d1dh, 00ba5a4dfh, 0a186f20fh, 02868f169h
  216.     dd 0dcb7da83h, 0573906feh, 0a1e2ce9bh, 04fcd7f52h, 050115e01h, 0a70683fah
  217.     dd 0a002b5c4h, 00de6d027h, 09af88c27h, 0773f8641h, 0c3604c06h, 061a806b5h
  218.     dd 0f0177a28h, 0c0f586e0h, 0006058aah, 030dc7d62h, 011e69ed7h, 02338ea63h
  219.     dd 053c2dd94h, 0c2c21634h, 0bbcbee56h, 090bcb6deh, 0ebfc7da1h, 0ce591d76h
  220.     dd 06f05e409h, 04b7c0188h, 039720a3dh, 07c927c24h, 086e3725fh, 0724d9db9h
  221.     dd 01ac15bb4h, 0d39eb8fch, 0ed545578h, 008fca5b5h, 0d83d7cd3h, 04dad0fc4h
  222.     dd 01e50ef5eh, 0b161e6f8h, 0a28514d9h, 06c51133ch, 06fd5c7e7h, 056e14ec4h
  223.     dd 0362abfceh, 0ddc6c837h, 0d79a3234h, 092638212h, 0670efa8eh, 0406000e0h
  224. sbox4    dd 03a39ce37h, 0d3faf5cfh, 0abc27737h, 05ac52d1bh, 05cb0679eh, 04fa33742h
  225.     dd 0d3822740h, 099bc9bbeh, 0d5118e9dh, 0bf0f7315h, 0d62d1c7eh, 0c700c47bh
  226.     dd 0b78c1b6bh, 021a19045h, 0b26eb1beh, 06a366eb4h, 05748ab2fh, 0bc946e79h
  227.     dd 0c6a376d2h, 06549c2c8h, 0530ff8eeh, 0468dde7dh, 0d5730a1dh, 04cd04dc6h
  228.     dd 02939bbdbh, 0a9ba4650h, 0ac9526e8h, 0be5ee304h, 0a1fad5f0h, 06a2d519ah
  229.     dd 063ef8ce2h, 09a86ee22h, 0c089c2b8h, 043242ef6h, 0a51e03aah, 09cf2d0a4h
  230.     dd 083c061bah, 09be96a4dh, 08fe51550h, 0ba645bd6h, 02826a2f9h, 0a73a3ae1h
  231.     dd 04ba99586h, 0ef5562e9h, 0c72fefd3h, 0f752f7dah, 03f046f69h, 077fa0a59h
  232.     dd 080e4a915h, 087b08601h, 09b09e6adh, 03b3ee593h, 0e990fd5ah, 09e34d797h
  233.     dd 02cf0b7d9h, 0022b8b51h, 096d5ac3ah, 0017da67dh, 0d1cf3ed6h, 07c7d2d28h
  234.     dd 01f9f25cfh, 0adf2b89bh, 05ad6b472h, 05a88f54ch, 0e029ac71h, 0e019a5e6h
  235.     dd 047b0acfdh, 0ed93fa9bh, 0e8d3c48dh, 0283b57cch, 0f8d56629h, 079132e28h
  236.     dd 0785f0191h, 0ed756055h, 0f7960e44h, 0e3d35e8ch, 015056dd4h, 088f46dbah
  237.     dd 003a16125h, 00564f0bdh, 0c3eb9e15h, 03c9057a2h, 097271aech, 0a93a072ah
  238.     dd 01b3f6d9bh, 01e6321f5h, 0f59c66fbh, 026dcf319h, 07533d928h, 0b155fdf5h
  239.     dd 003563482h, 08aba3cbbh, 028517711h, 0c20ad9f8h, 0abcc5167h, 0ccad925fh
  240.     dd 04de81751h, 03830dc8eh, 0379d5862h, 09320f991h, 0ea7a90c2h, 0fb3e7bceh
  241.     dd 05121ce64h, 0774fbe32h, 0a8b6e37eh, 0c3293d46h, 048de5369h, 06413e680h
  242.     dd 0a2ae0810h, 0dd6db224h, 069852dfdh, 009072166h, 0b39a460ah, 06445c0ddh
  243.     dd 0586cdecfh, 01c20c8aeh, 05bbef7ddh, 01b588d40h, 0ccd2017fh, 06bb4e3bbh
  244.     dd 0dda26a7eh, 03a59ff45h, 03e350a44h, 0bcb4cdd5h, 072eacea8h, 0fa6484bbh
  245.     dd 08d6612aeh, 0bf3c6f47h, 0d29be463h, 0542f5d9eh, 0aec2771bh, 0f64e6370h
  246.     dd 0740e0d8dh, 0e75b1357h, 0f8721671h, 0af537d5dh, 04040cb08h, 04eb4e2cch
  247.     dd 034d2466ah, 00115af84h, 0e1b00428h, 095983a1dh, 006b89fb4h, 0ce6ea048h
  248.     dd 06f3f3b82h, 03520ab82h, 0011a1d4bh, 0277227f8h, 0611560b1h, 0e7933fdch
  249.     dd 0bb3a792bh, 0344525bdh, 0a08839e1h, 051ce794bh, 02f32c9b7h, 0a01fbac9h
  250.     dd 0e01cc87eh, 0bcc7d1f6h, 0cf0111c3h, 0a1e8aac7h, 01a908749h, 0d44fbd9ah
  251.     dd 0d0dadecbh, 0d50ada38h, 00339c32ah, 0c6913667h, 08df9317ch, 0e0b12b4fh
  252.     dd 0f79e59b7h, 043f5bb3ah, 0f2d519ffh, 027d9459ch, 0bf97222ch, 015e6fc2ah
  253.     dd 00f91fc71h, 09b941525h, 0fae59361h, 0ceb69cebh, 0c2a86459h, 012baa8d1h
  254.     dd 0b6c1075eh, 0e3056a0ch, 010d25065h, 0cb03a442h, 0e0ec6e0eh, 01698db3bh
  255.     dd 04c98a0beh, 03278e964h, 09f1f9532h, 0e0d392dfh, 0d3a0342bh, 08971f21eh
  256.     dd 01b0a7441h, 04ba3348ch, 0c5be7120h, 0c37632d8h, 0df359f8dh, 09b992f2eh
  257.     dd 0e60b6f47h, 00fe3f11dh, 0e54cda54h, 01edad891h, 0ce6279cfh, 0cd3e7e6fh
  258.     dd 01618b166h, 0fd2c1d05h, 0848fd2c5h, 0f6fb2299h, 0f523f357h, 0a6327623h
  259.     dd 093a83531h, 056cccd02h, 0acf08162h, 05a75ebb5h, 06e163697h, 088d273cch
  260.     dd 0de966292h, 081b949d0h, 04c50901bh, 071c65614h, 0e6c6c7bdh, 0327a140ah
  261.     dd 045e1d006h, 0c3f27b9ah, 0c9aa53fdh, 062a80f00h, 0bb25bfe2h, 035bdd2f6h
  262.     dd 071126905h, 0b2040222h, 0b6cbcf7ch, 0cd769c2bh, 053113ec0h, 01640e3d3h
  263.     dd 038abbd60h, 02547adf0h, 0ba38209ch, 0f746ce76h, 077afa1c5h, 020756060h
  264.     dd 085cbfe4eh, 08ae88dd8h, 07aaaf9b0h, 04cf9aa7eh, 01948c25ch, 002fb8a8ch
  265.     dd 001c36ae4h, 0d6ebe1f9h, 090d4f869h, 0a65cdea0h, 03f09252dh, 0c208e69fh
  266.     dd 0b74e6132h, 0ce77e25bh, 0578fdfe3h, 03ac372e6h
  267.  
  268. if rnds eq 2
  269.   rounds    equ 32
  270.   PBox_size    equ 32+2
  271. else
  272.   if rnds eq 1
  273.     rounds    equ 16
  274.     PBox_size    equ 16+2
  275.   else
  276.     rounds    dw 16
  277.     PBox_size    dw 16+2
  278.   endif
  279. endif
  280.  
  281.         .CODE
  282.  
  283.  
  284. ; usefull macros
  285.  
  286. enciph_dxax MACRO boxnr4
  287.  
  288.         xor     edx, [pbox+boxnr4]        ; boxnr4 = PBox Nr * 4
  289.  
  290.     ror    edx,16
  291.  
  292.     mov    bl,dh
  293.     mov    ecx, [ebx*4+offset sbox1]    ; ECX = S[1,a]
  294.  
  295.     mov    bl, dl
  296.     add    ecx, [ebx*4+offset sbox2]    ; ECX = ECX + S[2,b]
  297.  
  298.     rol    edx,16
  299.  
  300.         mov     bl, dh                ; das 3te Byte -> c
  301.         xor     ecx, [ebx*4+offset sbox3]    ; ECX := ECX xor S[3,c]
  302.  
  303.         mov     bl, dl                ; das 4te Byte -> d
  304.         add     ecx, [ebx*4+offset sbox4]    ; ECX := ECX + S[4,d]
  305.  
  306.     xor    eax, ecx
  307. ENDM
  308.  
  309. enciph_axdx MACRO boxnr4
  310.  
  311.         xor     eax, [pbox+boxnr4]    ; boxnr4 = PBox Nr * 4
  312.     
  313.     ror    eax,16
  314.  
  315.     mov    bl,ah
  316.     mov    ecx, [ebx*4+offset sbox1]    ; ECX = S[1,a]
  317.  
  318.     mov    bl, al
  319.     add    ecx, [ebx*4+offset sbox2]    ; ECX = ECX + S[2,b]
  320.  
  321.     rol    eax,16
  322.  
  323.         mov     bl, ah            ; das 3te Byte -> c
  324.         xor     ecx, [ebx*4+offset sbox3]  ; ECX := ECX xor S[3,c]
  325.  
  326.         mov     bl, al            ; das 4te Byte -> d
  327.         add     ecx, [ebx*4+offset sbox4]    ; ECX := ECX + S[4,d]
  328.  
  329.     xor    edx, ecx
  330. ENDM
  331.  
  332.  
  333.  
  334.  
  335.  
  336. ; BLOWFISH_GETBOXPOINTER - simply returns the address of the first
  337. ;               pbox, _assumes_ that the boxes are linked !
  338. ; <- Pointer
  339.  
  340. Blowfish_GetBoxPointer proc
  341.  
  342.         mov     dx, seg pbox    ; when _DATA segments are combined same as DS
  343.         mov     ax, offset pbox    ; (as in Pascal). In some cases not (!)
  344.         ret
  345.  
  346. Blowfish_GetBoxPointer endp
  347.  
  348. ; BLOWFISH_GetBoxes - copies the contents of the boxes to pBuffer, with a
  349. ;                     minimum border of 8 bytes, saves no registers
  350. ; -> pBuffer : Pointer
  351.  
  352. Blowfish_GetBoxes proc
  353.  
  354.     push    bp
  355.     mov    bp, sp
  356.     mov    bx,es
  357.  
  358.         mov     cx, PSBOX_SIZE        ; Size of P+SBoxes in DWords
  359.         les     di, [BP+sofs+6]     ; pBuffer is target
  360.         mov     si, offset pbox     ; Boxes are source
  361.  
  362.         cld
  363.     rep    movsd
  364.  
  365.     mov    es,bx
  366.     pop    bp
  367.     ret    4
  368.  
  369. Blowfish_GetBoxes endp
  370.  
  371. ; BLOWFISH_SetBoxes - copies the contents of pBuffer to the boxes, with a
  372. ;            minimum border of 8 bytes, saves no registers
  373. ; -> pBuffer : Pointer
  374.  
  375. Blowfish_SetBoxes proc
  376.  
  377.     push    bp
  378.     mov    bp, sp
  379.     mov    bx,es
  380.     mov    dx,ds
  381.     mov    es,dx
  382.  
  383.         mov     cx, PSBOX_SIZE        ; Size of P+SBoxes in DWords
  384.         lds     si, [BP+sofs+6]        ; Buffer is source
  385.         mov     di, offset pbox        ; Boxes are target
  386.  
  387.         cld
  388.     rep    movsd
  389.  
  390.     mov    ds,dx
  391.     mov    es,bx
  392.     pop    bp
  393.     ret    4
  394.  
  395. Blowfish_SetBoxes endp
  396.  
  397.  
  398.  
  399. ; the engine...
  400.  
  401.  
  402.  
  403. ; BLOWFISH_ENCIPHER - this function encrypts a 64bit data elememt,
  404. ;              saves no registers, so it can be adjusted to the
  405. ;              maximum speed to every caller,
  406. ;              registers EAX,EBX,ECX,EDX will be destroyed
  407. ; <-> EDX:EAX - the 64bit data element (left:right)
  408.  
  409. blowfish_encipher proc near
  410.  
  411.     xor    ebx,ebx        ; needed later
  412.  
  413. if noLOOP eq 1            ; very fast code without LOOP`s
  414.     PBNr = 0
  415.     REPT 8
  416.      enciph_dxax PBNr
  417.      PBNr = PBNr + 4
  418.      enciph_axdx PBNr
  419.      PBNr = PBNr + 4
  420.     endm
  421.   if rnds eq 3
  422.     cmp    rounds,16
  423.     jne    short be32
  424.   endif
  425.   ife rnds eq 2
  426.     xchg    eax, edx
  427.         xor     eax, pbox+PBNr
  428.         xor     edx, pbox+PBNr+4
  429.     ret
  430.   endif
  431.   ife rnds eq 1
  432. be32:    REPT 8
  433.      enciph_dxax PBNr
  434.      PBNr = PBNr + 4
  435.      enciph_axdx PBNr
  436.      PBNr = PBNr + 4
  437.     endm
  438.     xchg    eax, edx
  439.         xor     eax, pbox+PBNr
  440.         xor     edx, pbox+PBNr+4
  441.     ret
  442.   endif
  443. else                ; or with LOOP`s
  444.     push    si
  445.     push    di
  446.     mov    si,0
  447.     mov    di,rounds       ; 16 or 32
  448.     shl    di,2        ; * 4
  449. bel:    enciph_dxax si
  450.     xchg    eax, edx
  451.     add    si,4
  452.     cmp    si,di
  453.     jne    bel
  454.     xchg    eax, edx
  455.         xor     eax, [pbox+si]
  456.         xor     edx, [pbox+4+si]
  457.     pop    di
  458.     pop    si
  459.     ret
  460. endif
  461.  
  462. blowfish_encipher endp
  463.  
  464.  
  465.  
  466. ; BLOWFISH_DECIPHER - this function decrypts a 64bit data elememt,
  467. ;              saves no registers, so it can be adjusted to the
  468. ;              maximum speed to every caller,
  469. ;              registers EAX, EBX, ECX and EDX will be destroyed
  470. ; <-> EDX:EAX - the 64bit data element (left:right)
  471.  
  472. ; for the most curious fact we can use the "enciph" macro for
  473. ; the decryption again...
  474.  
  475. blowfish_decipher proc near
  476.  
  477.     xor    ebx,ebx        ; needed later
  478.  
  479. if noLOOP eq 1            ; without LOOP`s
  480.   if rnds eq 3
  481.     cmp    rounds,16
  482.     je    bd16
  483.   endif
  484.   ife rnds eq 1
  485.     PBNr = 33*4
  486.     REPT 8
  487.      enciph_dxax PBNr
  488.      PBNr = PBNr - 4
  489.      enciph_axdx PBNr
  490.      PBNr = PBNr - 4
  491.     endm
  492.   endif
  493. bd16:
  494.     PBNr = 17*4
  495.     REPT 8
  496.      enciph_dxax PBNr
  497.      PBNr = PBNr - 4
  498.      enciph_axdx PBNr
  499.      PBNr = PBNr - 4
  500.     endm
  501. else                 ; or with LOOP`s
  502.     push    si
  503.     mov    si,rounds    ; 16 or 32
  504.     inc    si        ; = 17 or 33
  505.     shl    si,2        ; * 4
  506. bdl:    enciph_dxax si
  507.     xchg    eax, edx
  508.     sub    si,4
  509.     cmp    si,1*4
  510.     jne    bdl
  511.     pop    si
  512. endif
  513.     xchg    eax, edx
  514.         xor     eax, pbox+(1*4)
  515.         xor     edx, pbox+(0*4)
  516.         ret
  517.  
  518. blowfish_decipher endp
  519.  
  520.  
  521.  
  522. ; BLOWFISH_ECBENCRYPT - encrypts wCount bytes, with a minimum border of
  523. ;            8 bytes, saves no registers
  524. ; -> pBuffer : Pointer, wCount : Word
  525.  
  526. Blowfish_ECBEncrypt proc
  527.  
  528.     push    bp
  529.     mov    bp, sp
  530.  
  531.         mov     cx, [BP+sofs+6]      ; Number of Bytes (wCount) to encrypt
  532.         les     di, [BP+sofs+8]      ; pBuffer as target
  533.         lfs     si, [BP+sofs+8]      ; pBuffer as source
  534.  
  535.         shr     cx, 3                ; Change Byte- to DWord-counter
  536.         cld
  537. @@EDlp:
  538.         push    cx
  539.         mov     edx, fs:[si]    ; load 64bit Data EDX:EAX 
  540.         mov     eax, fs:[si+4]  ; (EDX is the lower DWord !)
  541.         add     si, 8
  542.  
  543.         call    blowfish_encipher       ; encrypt
  544.  
  545.         mov     es:[di], edx    ; save the result
  546.         add     di, 4
  547.     stosd
  548.  
  549.         pop     cx
  550.         dec     cx              ; (faster than LOOP on 386)
  551.         jnz     @@EDlp
  552.  
  553.     pop    bp
  554.     ret    6
  555.  
  556. Blowfish_ECBEncrypt endp
  557.  
  558.  
  559.  
  560.  
  561. ; BLOWFISH_ECBDECRYPT - decrypts wCount bytes, with a minimum border of
  562. ;            8 bytes, saves no registers
  563. ; -> pBuffer : Pointer, wCount : Word
  564.  
  565. Blowfish_ECBDecrypt proc
  566.  
  567.     push    bp
  568.     mov    bp, sp
  569.  
  570.         mov     cx, [BP+sofs+6]      ; Number of Bytes
  571.         les     di, [BP+sofs+8]      ; pBuffer is target
  572.         lfs     si, [BP+sofs+8]      ; and source
  573.  
  574.         shr     cx, 3           ; Byte to DWord counter
  575.         cld
  576.  
  577. @@DDlp:
  578.         push    cx
  579.         mov     edx, fs:[si]    ; load 64bit Data EDX:EAX 
  580.         mov     eax, fs:[si+4]
  581.         add     si, 8
  582.  
  583.         call    blowfish_decipher       ; decrypt
  584.  
  585.         mov     es:[di], edx    ; save result
  586.         add     di, 4
  587.     stosd
  588.  
  589.         pop     cx
  590.         dec     cx
  591.         or      cx, cx
  592.         jnz     @@DDlp
  593.  
  594.     pop    bp
  595.     ret    6
  596.  
  597. Blowfish_ECBDecrypt endp
  598.  
  599.  
  600.  
  601. ; BLOWISH_CBCENCRYPT - encrypts wCount bytes, with a minimum border of 8 bytes,
  602. ;               uses the CBC method, returns a 32bit crc, saves no
  603. ;               registers, except of DS
  604. ; -> pBuffer : Pointer, wCount : Word, var lCBClo, lCBChi : Longint
  605.  
  606. Blowfish_CBCEncrypt proc
  607.  
  608.     push    bp
  609.     mov    bp, sp
  610.         cld
  611.  
  612.         mov     cx, ds          ; read CBC-String ...
  613.         lds     si, [BP+sofs+10]
  614.         lodsd
  615.         push    eax
  616.         lds     si, [BP+sofs+6]      ; ... save it on the Stack
  617.         lodsd
  618.         push    eax
  619.         mov     ds, cx
  620.  
  621.         mov     cx, [BP+sofs+14]     ; Number of Bytes
  622.         les     di, [BP+sofs+16]     ; pBuffer is target
  623.         lfs     si, [BP+sofs+16]     ; and source
  624.  
  625.         shr     cx, 3           ; Byte to DWord counter
  626.  
  627. @@CBCEDlp:
  628.         mov     edx, fs:[si]    ; load 64bit Data in EDX:EAX 
  629.         mov     eax, fs:[si+4]
  630.         add     si, 8
  631.  
  632.         pop     ebx             ; get CBC-String from Stack and combine with 
  633.         xor     edx, ebx        ; Data
  634.         pop     ebx
  635.         xor     eax, ebx
  636.  
  637.         push    cx
  638.         call    blowfish_encipher       ; encrypt
  639.         pop     cx
  640.  
  641.         push    eax             ; Result is the new CBC-String,
  642.         push    edx             ; put it on the stack again
  643.  
  644.         mov     es:[di], edx    ; save encrypted Data
  645.         add     di, 4
  646.     stosd
  647.  
  648.         dec     cx
  649.         jnz     @@CBCEDlp
  650.  
  651.         pop     ecx             ; return CBC-String
  652.         pop     ebx
  653.         lgs     di, [BP+sofs+6]
  654.         mov     gs:[di], ecx
  655.         lgs     di, [BP+sofs+10]
  656.         mov     gs:[di], ebx
  657.  
  658.     pop    bp
  659.     ret    14
  660.  
  661. Blowfish_CBCEncrypt endp
  662.  
  663.  
  664.  
  665.  
  666. ; BLOWFISH_CBCDECRYPT - decrypts wCount bytes, with a minimum border of 8 bytes,
  667. ;            uses the CBC method, saves no registers, except of DS
  668. ; -> pBuffer : Pointer, wCount : Word, var lCBClo, lCBChi : Longint
  669.  
  670. Blowfish_CBCDecrypt proc
  671.  
  672.     push    bp
  673.     mov    bp, sp
  674.         cld
  675.  
  676.         mov     cx, ds          ; get CBC-String ...
  677.         lds     si, [BP+sofs+10]
  678.         lodsd
  679.         push    eax
  680.         lds     si, [BP+sofs+6]      ; ...and put it on the stack
  681.         lodsd
  682.         push    eax
  683.         mov     ds, cx
  684.  
  685.         mov     cx, [BP+sofs+14]      ; Number of Bytes
  686.         les     di, [BP+sofs+16]      ; pBuffer is target
  687.         lfs     si, [BP+sofs+16]      ; and source
  688.  
  689.         shr     cx, 3           ; Byte to DWord counter
  690.  
  691. @@CBCDDlp:
  692.         mov     edx, fs:[si]    ; load 64bit Data in EDX:EAX 
  693.         mov     eax, fs:[si+4]
  694.         add     si, 8
  695.  
  696.         shl     edi, 16         ; now it get's tricky (Stack-Swapping)...
  697.         mov     di, cx
  698.         pop     ecx             ; Get CBC-String from Stack 
  699.         pop     ebx
  700.         push    eax             ; The new CBC-String is the encryptet
  701.         push    edx             ; Data, put it on the stack
  702.         push    ebx             ; save the aktuel CBC-String 
  703.         push    ecx             ; on the Stack
  704.         mov     cx, di          ; get CX back
  705.         shr     edi, 16
  706.  
  707.         push    cx
  708.         call    blowfish_decipher       ; decrypt
  709.         pop     cx
  710.  
  711.         pop     ebx             ; reverse Data / CBC combination
  712.         xor     edx, ebx
  713.         pop     ebx
  714.         xor     eax, ebx
  715.  
  716.         mov     es:[di], edx    ; save decrypted Data
  717.         add     di, 4
  718.     stosd
  719.  
  720.         dec     cx
  721.         jnz     @@CBCDDlp
  722.  
  723.         pop     ecx             ; return CBC
  724.         pop     ebx
  725.         lgs     di, [BP+sofs+6]
  726.         mov     gs:[di], ecx
  727.         lgs     di, [BP+sofs+10]
  728.         mov     gs:[di], ebx
  729.  
  730.     pop    bp
  731.     ret    14
  732.  
  733. Blowfish_CBCDecrypt endp
  734.  
  735.  
  736.  
  737.  
  738.  
  739. ; BLOWFISH_INIT - initalises the boxes with a defined key
  740. ; -> key : Pointer, length : Word
  741.  
  742. Blowfish_Init proc
  743.  
  744.     push    bp
  745.     mov    bp, sp
  746.  
  747.     ; xor the pboxes with the key...
  748.  
  749.     mov    dx, [BP+sofs+6]    ; load the key's length
  750.     or    dx, dx
  751.     jz    short @@BIexit    ; avoid zero cases
  752.  
  753.     mov    ax, ds        ; ES = DS
  754.     mov    es, ax
  755.         mov     cx, PBOX_SIZE    ; set counter
  756.   if rnds eq 3
  757.     push    cx        ; für 2te Runde merken
  758.   endif
  759.     lds    si, [BP+sofs+8]    ; load the key pointer
  760.     mov    bx, si        ; (and save the offset for within the loop)
  761.         mov     bp, dx          ; (we don't need BP any more }
  762.         mov     di, offset pbox
  763.         cld
  764. @@BIlp0:
  765.     push    cx
  766.     mov    cx, 4        ; built a dword in EAX in MSB byte order
  767. @@BIlp1:
  768.     shl    eax, 8
  769.     lodsb
  770.     dec    dx        ; cycle through the key
  771.     jnz    short @@BInocycle
  772.     mov    si, bx        ; (reload the key start address and length)
  773.         mov     dx, bp
  774. @@BInocycle:
  775.     dec    cx
  776.     jnz    @@BIlp1
  777.  
  778.     xor    es:[di], eax    ; xor with the actual pbox
  779.         add     di, 4           ; next pbox
  780.         pop     cx
  781.     dec    cx
  782.     jnz    @@BIlp0
  783.  
  784.     mov    ax, es        ; restore DS
  785.     mov    ds, ax
  786.  
  787.     ; now encrypt all the boxes starting with
  788.     ; a so called "all zero-string"
  789.  
  790.     xor    eax, eax        ; create the zero-string
  791.     mov    edx, eax
  792.  
  793.   if rnds eq 3
  794.         pop     si            ; PBOX_SIZE (CX in use, SI as counter)
  795.     shr    si, 1            ; / 2
  796.   else
  797.       mov    si,PBox_size / 2
  798.   endif
  799.     mov    di, offset pbox     ; encrypt boxes...
  800. @@BIlp2:
  801.         call    blowfish_encipher    ; (destroys ECX and EBX)
  802.     mov    [di], edx
  803.     add    di, 4
  804.     stosd                ; (ES = DS)
  805.     dec    si
  806.     jnz    @@BIlp2
  807.  
  808.         mov     si, (4*256)/2           ; SBox_size / 2
  809.     mov    di, offset sbox1     ; encrypt boxes...
  810. @@BIlp3:
  811.         call    blowfish_encipher    ; (destroys ECX and EBX)
  812.     mov    [di], edx
  813.     add    di, 4
  814.     stosd                ; (ES = DS)
  815.     dec    si
  816.     jnz    @@BIlp3
  817.  
  818.  
  819. @@BIexit:
  820.     pop    bp
  821.     ret    6
  822.  
  823. Blowfish_Init endp
  824.  
  825.  
  826.  
  827. ; BLOWFISH_DONE - simply clears all the boxes to let no sensitive data
  828. ;          left in memory after the applications is finished
  829.  
  830. Blowfish_Done proc
  831.  
  832.         push    es
  833.         push    ds
  834.         pop     es
  835.         mov     di, offset pbox         ; fast 32 Bit clear
  836.         mov     cx, PSBOX_SIZE
  837.         xor     eax, eax
  838.         cld
  839.         rep     stosd
  840.         pop     es
  841.         ret
  842.  
  843. Blowfish_Done endp
  844.  
  845.  
  846.  
  847. ; BLOWFISH_SETROUNDS - sets the rounds Blowfish has to go: 16 or 32
  848.  
  849. Blowfish_SetRounds proc
  850.  
  851.     push    bp
  852.     mov    bp, sp
  853.   if rnds eq 3
  854.     mov    ax, [BP+sofs+6]    ; # of rounds
  855.      if noLoop eq 1
  856.     cmp    ax,16        ; if enrolled only 16 oder 32 Rounds allowed
  857.     je    br1
  858.     cmp    ax,32
  859.     jne    brexit
  860.      else
  861.     and    ax,0fffeh
  862.     cmp    ax,0        ; else you can use all from 2 to 32 in
  863.     je    brexit        ; steps of 2
  864.     cmp    ax,32
  865.     ja    brexit
  866.      endif
  867. br1:    mov    rounds,ax
  868.     add    ax,2
  869.     mov    PBox_size,ax
  870.   endif
  871.  
  872. brexit:    mov    ax, rounds    ; Return the number of rounds actual used
  873.     pop     bp
  874.         ret    2
  875.  
  876. Blowfish_SetRounds endp
  877.  
  878.  
  879. ; Blowfish_WeakKey detects "bad" passwords
  880.  
  881. Blowfish_WeakKey proc
  882.     push    es
  883.     push    ds
  884.     pop    es
  885.     cld
  886.     mov    dx,1            ; assume WeakKey
  887.     mov    bx,offset sbox1
  888.     mov    si,offset sbox1 + 4*4*256    ; all SBoxes (4*4*256 Bytes)
  889.  
  890. wkl:    mov    eax,[bx]        ; get DWord
  891.     add    bx,4            ; position to next
  892.     mov    di,bx            ; start compare here
  893.     mov    cx,si            ; Number of compares = End
  894.     sub    cx,bx            ; minus next Position
  895.     je    bfwok            ; Same?, Then ready
  896.     shr    cx,2            ; count in in DWords
  897.     repne    scasd            ; search
  898.     je    bfwke            ; found? yes -> key is weak
  899.     jmp    short wkl
  900.  
  901. bfwok:    dec    dx            ; Key is not weak
  902. bfwke:    mov    ax,dx
  903.     pop    es
  904.     ret
  905. Blowfish_WeakKey endp
  906.  
  907.  
  908.         _end
  909.  
  910.